Compute gross primary production modifiers
!! Compute gross primary production modifiers !|author: <a href="mailto:giovanni.ravazzani@polimi.it">Giovanni Ravazzani</a> ! license: <a href="http://www.gnu.org/licenses/">GPL</a> ! !### History ! ! current version 1.0 - 2nd May 2019 ! ! | version | date | comment | ! |----------|-------------|----------| ! | 1.0 | 2/May/2019 | Original code | ! !### License ! license: GNU GPL <http://www.gnu.org/licenses/> ! !### Module Description ! Routines to compute gross primary production modifiers ! Implemented modifiers: ! ! 1. Age modifier [[Agemod]] ! ! 2. CO<sub>2</sub> modifier [[CO2mod]] ! ! 3. Soil water content modifier [[SWCmod]] ! ! 4. Air temperature modifier [[TEMPmod]] ! ! 5. Vapor pressure deficit modifier [[VPDmod]] ! MODULE PlantsModifiers ! Modules used: USE DataTypeSizes, ONLY : & ! Imported Type Definitions: short, float USE LogLib, ONLY: & !Imported routines: Catch IMPLICIT NONE !global routines: PUBLIC :: SWCmod PUBLIC :: AGEmod PUBLIC :: TEMPmod PUBLIC :: VPDmod PUBLIC :: CO2mod !local routines: !======= CONTAINS !======= !============================================================================== !| Description: ! compute the age modifier. It modulates the maximum potential growth during the ! different stages of the vegetation life cycle as trees in the early stages ! are not as vigorous as mature trees ! ! Reference: ! ! Peng, C., J. Liu, Q. Dang, M. J. Apps, and H. Jiang, 2002: TRIPLEX: A generic ! hybrid model for predicting forest growth and carbon and nitrogen dynamics. ! Ecol. Modell., 153 (1–2), 109–130. FUNCTION AGEmod & ! (age, agemax) & ! RESULT (f) IMPLICIT NONE !arguments with intent(in): REAL (KIND = float), INTENT(IN) :: age !!actual age (years) REAL (KIND = float), INTENT(IN) :: agemax !! maximum age (years) !local declarations: REAL (KIND = float) :: f !---------------------------------------end of declarations-------------------- !compute modifier !IF ( age < 0.2 * agemax ) THEN ! f = 0.7 + 0.3 * age / ( 0.2 * agemax) !ELSE ! f = 1. + MAX (0., ((age - 0.2 * agemax) / (0.95 * agemax) ) ** 3. ) !END IF f = ( 1. / (1. + ( ( age / agemax ) / 0.95 ) ) )**4. !final boundary check IF ( f > 1.) THEN f = 1. END IF IF ( f < 0.) THEN f = 0. END IF RETURN END FUNCTION AGEmod !============================================================================== !| Description: ! soil water content modifier ! ! Reference: ! ! Cox, P. M., C. Huntingford, and R. J. Harding, 1998: A canopy conductance ! and photosynthesis model for use in a GCM land surface scheme. ! J. Hydrol., 212–213, 79–94 ! FUNCTION SWCmod & ! (swc, wp, fc, theta) & ! RESULT (f) IMPLICIT NONE !Arguments with intent (in): REAL (KIND = float), INTENT (IN) :: swc !! actual soil water content [m3/m3] REAL (KIND = float), INTENT (IN) :: wp !! soil wilting point [m3/m3] REAL (KIND = float), INTENT (IN) :: fc !! soil field capacity [m3/m3] REAL (KIND = float), INTENT (IN) :: theta !! empirical parameter to compute soil water content modifier !local declarations: REAL (KIND = float) :: f REAL (KIND = float) :: beta !---------------------------------------end of declarations-------------------- !compute beta IF ( swc <= wp ) THEN beta = 0. ELSE IF ( swc > wp .AND. swc < fc ) THEN beta = ( swc - wp ) / ( fc - wp ) ELSE !swc >= fc beta = 1. END IF !compute modifier f = ( 1. - EXP ( - beta * theta) ) / ( 1. - EXP ( - theta) ) !final boundary check IF ( f > 1.) THEN f = 1. END IF IF ( f < 0.) THEN f = 0. END IF RETURN END FUNCTION SWCmod !============================================================================== !| Description: ! compute air temperature modifier. The growth and dormant stages of ! vegetation are related to the annual cycle of air temperature. ! Maximum growth will happen at optimal temperatures Topt and ! will stop when temperatures drop below or exceed certain temperature ! thresholds, Tmin and Tmax, respectively. ! ! Reference: ! ! Landsberg, J. J., and R. H. Waring, 1997: A generalised model of forest ! productivity using simplified concepts of radiation-use efficiency, ! carbon balance and partitioning. For. Ecol. Manage., 95, 209–228. FUNCTION TEMPmod & ! (Ta, Tmin, Tmax, Topt) & ! RESULT (f) IMPLICIT NONE !Arguments with intent(in): REAL (KIND = float), INTENT(IN) :: Ta ! current air temperature [°C] REAL (KIND = float), INTENT(IN) :: Tmin ! minimum temperature for vegetation growing [°C] REAL (KIND = float), INTENT(IN) :: Tmax ! maximum temperature for vegetation growing [°C] REAL (KIND = float), INTENT(IN) :: Topt ! optimum temperature for vegetation growing [°C] !local declarations: REAL (KIND = float) :: f REAL (KIND = float) :: Tair !---------------------------------------end of declarations-------------------- IF ( Topt < Tmin) THEN CALL Catch ('error', 'PlantsModifiers', 'Topt < Tmin cannot compute temperature modifier') END IF IF ( Topt > Tmax) THEN CALL Catch ('error', 'PlantsModifiers', 'Topt > Tmax cannot compute temperature modifier') END IF !set tair IF (Ta > Tmax ) THEN Tair = Tmax CALL Catch ('warning', 'PlantsModifiers', 'Tair > Tmax Tair set to Tmax') ELSE IF (Ta < Tmin) THEN Tair = Tmin CALL Catch ('warning', 'PlantsModifiers', 'Tair < Tmin Tair set to Tmin') ELSE Tair = Ta END IF !compute modifier f = ( Tair - Tmin ) / ( Topt - Tmin ) * & ( ( Tmax - Tair ) / ( Tmax - Topt ) ) ** ( (Tmax -Topt) / (Topt - Tmin) ) !final boundary check IF ( f > 1.) THEN f = 1. END IF IF ( f < 0.) THEN f = 0. END IF RETURN END FUNCTION TEMPmod !============================================================================== !| Description: ! compute vapor pressure deficit modifier. ! ! References: ! ! Landsberg, J. J., and R. H. Waring, 1997: A generalised model of forest ! productivity using simplified concepts of radiation-use efficiency, ! carbon balance and partitioning. For. Ecol. Manage., 95, 209–228. ! ! Dingman, S. L., 2002: Physical Hydrology. Prentice Hall, 646 pp ! FUNCTION VPDmod & ! (Ta, RH, kd) & ! RESULT (f) IMPLICIT NONE !Arguments with intent(in): REAL (KIND = float), INTENT(IN) :: Ta ! current air temperature [°C] REAL (KIND = float), INTENT(IN) :: RH ! air relative humidity [0-1] REAL (KIND = float), INTENT(IN) :: kd ! Stomatal response to VPD [mbar] !local declarations: REAL (KIND = float) :: f REAL (KIND = float) :: estar !!saturation vapor pressure [mbar] REAL (KIND = float) :: vpd !!vapor pressure deficit [mbar] !---------------------------------------end of declarations-------------------- !compute saturation vapor pressure in the air (Dingman, 2002) [mbar] estar = 6.1076 * EXP ( (17.269 * Ta) / (Ta + 237.3) ) !compute vapor pressure deficit vpd = estar * ( 1. - RH ) !compute modifier f = EXP ( - kd * vpd) !final boundary check IF ( f > 1.) THEN f = 1. END IF IF ( f < 0.) THEN f = 0. END IF RETURN END FUNCTION VPDmod !============================================================================== !| Description: ! compute CO<sub>2</sub>2 modifier. ! ! References: ! ! Veroustraete, F., Sabbe, H. and Eerens, H. (2002) ‘Estimation of carbon ! mass fluxes over Europe using the C-Fix model and Euroflux data’, ! Remote Sensing of Environment, 83(3), pp. 376–399. ! doi: 10.1016/S0034-4257(02)00043-3. FUNCTION CO2mod & ! (co2, age) & ! RESULT (f) IMPLICIT NONE !arguments with intent(in): REAL (KIND = float), INTENT(IN) :: co2 !!CO2 concentration (ppm) REAL (KIND = float), INTENT(IN) :: age !! plant age (year) !local declarations: REAL (KIND = float) :: f REAL (KIND = float) :: fCalphax !---------------------------------------end of declarations-------------------- IF (age == 2.) THEN fCalphax = 1. ELSE fCalphax = age / (2. - age) END IF f = fCalphax * co2 / (350. * (fCalphax - 1.) + co2) RETURN END FUNCTION CO2mod END MODULE PlantsModifiers